home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
smaltalk
/
manchest.lha
/
MANCHESTER
/
manchester
/
2.2
/
Calculator.st
< prev
next >
Wrap
Text File
|
1993-07-24
|
21KB
|
811 lines
" NAME Calculator
AUTHOR TPH@cs.man.ac.uk
FUNCTION faster & better & keyboard drivable
ST-VERSIONS 2.2
PREREQUISITES
CONFLICTS
DISTRIBUTION world
VERSION 1.1
DATE 22 Jan 1989
SUMMARY Calculator
is a new version of the credit-card calculator. It is
significantly faster than the previous version, as well as
having much less code! Also, a couple of new features: a
`raise-to-power' button, and bindings to keyboard characters
(so that you can type at it!). Tested with VI2.2 and VI2.3.
Could probably be made to work with earlier versions. TPH,
11/2/89. (2.2)
"!
MouseMenuController subclass: #CalculatorController
instanceVariableNames: ''
classVariableNames: 'CalculatorYellowButtonMenu CalculatorYellowButtonMessages '
poolDictionaries: ''
category: 'Interface-Calculator'!
!CalculatorController methodsFor: 'initialize-release'!
initialize
super initialize.
self initializeYellowButtonMenu! !
!CalculatorController methodsFor: 'control defaults'!
isControlActive
^super isControlActive & sensor blueButtonPressed not! !
!CalculatorController methodsFor: 'menu messages'!
changeDigitLength
"Change the number of digits displayed."
| answerString |
answerString _ FillInTheBlank
request: 'Number of digits to be displayed?'
initialAnswer: model noOfDigits printString.
answerString isEmpty ifFalse: [
model noOfDigits: (Number readFrom: (ReadStream on: answerString))]!
setLeftJustify
"Display as left-justified."
model leftJustify ifFalse: [model leftJustify: true]!
setRightJustify
"Display as right-justified."
model leftJustify ifTrue: [model leftJustify: false]! !
!CalculatorController methodsFor: 'private'!
initializeYellowButtonMenu
"Initialize the middle button menu."
self
yellowButtonMenu: CalculatorYellowButtonMenu
yellowButtonMessages: CalculatorYellowButtonMessages! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
CalculatorController class
instanceVariableNames: ''!
!CalculatorController class methodsFor: 'class initialization'!
initialize
"Specify the Yellow button menu and messages."
"CalculatorController initialize."
CalculatorYellowButtonMenu _ PopUpMenu
labels: ' Digit Length \ Left Justify \ Right Justify ' withCRs
lines: #(1).
CalculatorYellowButtonMessages _ #(changeDigitLength setLeftJustify setRightJustify).! !
CalculatorController initialize!
Model subclass: #Calculator
instanceVariableNames: 'displayValue accumulatorValue currentOperation doneOperation noOfDigits errorFlag pointPlaces trailingZeros leftJustify '
classVariableNames: 'DefaultNoOfDigits '
poolDictionaries: ''
category: 'Interface-Calculator'!
!Calculator methodsFor: 'initialize-release'!
initialize
"Initialize the receiver."
displayValue _ 0.
accumulatorValue _ 0.
currentOperation _ nil.
doneOperation _ true.
errorFlag _ false.
pointPlaces _ 0.
trailingZeros _ 0.
leftJustify _ true.
noOfDigits _ DefaultNoOfDigits! !
!Calculator methodsFor: 'accessing'!
displayValue
"Answers with the current display value."
^displayValue!
errorFlag
"Answer the error flag value."
^errorFlag!
leftJustify
"Answer the current value of the left justify flag."
^leftJustify!
leftJustify: aBoolean
"Set the current value of the left justify flag."
leftJustify _ aBoolean.
self changed!
noOfDigits
"Answer the number of digits represented."
^noOfDigits!
noOfDigits: aNumber
"Sets the number of digits represented to aNumber."
noOfDigits _ aNumber.
self changed!
trailingZeros
"Answer the number of trailing zeros."
^trailingZeros! !
!Calculator methodsFor: 'operation keys'!
add
"Make the current operation addition."
self doOperation.
currentOperation _ #addition.!
changeSign
"Change the sign of the value in the display register."
self makeDisplay: displayValue negated!
clear
"Clear the error flag. Clear the display and accumulator registers."
errorFlag _ false.
pointPlaces _ 0.
trailingZeros _ 0.
accumulatorValue _ 0.
currentOperation _ nil.
self makeDisplay: 0!
clearEntry
"Zero the display register."
pointPlaces _ 0.
trailingZeros _ 0.
self makeDisplay: 0!
divide
"Make the current operation division."
self doOperation.
currentOperation _ #division!
equals
"Perform the current operation, putting the answer in
the accumulator. Display the answer."
self performOperation: currentOperation.
self makeDisplay: accumulatorValue.
doneOperation _ true.
trailingZeros _ 0.
currentOperation _ nil!
multiply
"Make the current operation multiplication."
self doOperation.
currentOperation _ #multiplication!
point
"Insert a decimal point. Sets the number of decimal places to 1."
pointPlaces = 0 ifTrue: [pointPlaces _ 1]!
raiseTo
"Make the current operation raise-to-power."
self doOperation.
currentOperation _ #raiseTo!
subtract
"Make the current operation subtraction."
self doOperation.
currentOperation _ #subtraction.! !
!Calculator methodsFor: 'digit keys'!
add0
"Add 0 to the display value."
pointPlaces > 0 ifTrue: [trailingZeros _ trailingZeros + 1].
self addToDisplay: 0.!
add1
"Add 1 to the display value."
trailingZeros _ 0.
self addToDisplay: 1.!
add2
"Add 2 to the display value."
trailingZeros _ 0.
self addToDisplay: 2.!
add3
"Add 3 to the display value."
trailingZeros _ 0.
self addToDisplay: 3.!
add4
"Add 4 to the display value."
trailingZeros _ 0.
self addToDisplay: 4.!
add5
"Add 5 to the display value."
trailingZeros _ 0.
self addToDisplay: 5.!
add6
"Add 6 to the display value."
trailingZeros _ 0.
self addToDisplay: 6.!
add7
"Add 7 to the display value."
trailingZeros _ 0.
self addToDisplay: 7.!
add8
"Add 8 to the display value."
trailingZeros _ 0.
self addToDisplay: 8.!
add9
"Add 9 to the display value."
trailingZeros _ 0.
self addToDisplay: 9.! !
!Calculator methodsFor: 'private'!
addToDisplay: aNumber
"Adds a number to the display value. The model has
changed."
| temp |
doneOperation ifTrue: [
displayValue _ 0.
doneOperation _ false].
displayValue < 0
ifTrue: [temp _ aNumber negated]
ifFalse: [temp _ aNumber].
pointPlaces ~= 0
ifTrue: [
self makeDisplay: displayValue +
(temp / (10 raisedToInteger: pointPlaces)).
pointPlaces _ pointPlaces + 1]
ifFalse: [self makeDisplay: displayValue * 10 + temp]!
doOperation
"Do the current operation (if any). Update the display
and accumulator."
currentOperation notNil ifTrue: [
self performOperation: currentOperation.
self makeDisplay: accumulatorValue].
trailingZeros _ 0.
pointPlaces _ 0.
doneOperation _ true.
accumulatorValue _ displayValue.!
makeDisplay: aNumber
"Makes aNumber the display value. The model has changed."
aNumber >= (10 raisedToInteger: noOfDigits)
ifTrue: [errorFlag _ true]
ifFalse: [displayValue _ aNumber].
self changed!
performOperation: aSymbol
"Perform the operation given by aSymbol."
aSymbol = #addition ifTrue: [
accumulatorValue _ accumulatorValue + displayValue].
aSymbol = #subtraction ifTrue: [
accumulatorValue _ accumulatorValue - displayValue].
aSymbol = #multiplication ifTrue: [
accumulatorValue _ accumulatorValue * displayValue].
aSymbol = #division ifTrue: [
displayValue = 0
ifTrue: [errorFlag _ true.]
ifFalse: [accumulatorValue _ accumulatorValue / displayValue]].
aSymbol = #raiseTo ifTrue: [
accumulatorValue _ accumulatorValue raisedTo: displayValue].
pointPlaces _ 0! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
Calculator class
instanceVariableNames: ''!
!Calculator class methodsFor: 'instance creation'!
new
"Create a new initialized instance of the receiver."
^super new initialize!
new: aNumber
"Create a new instance of the receiver, with aNumber digits."
^self new noOfDigits: aNumber! !
!Calculator class methodsFor: 'class initialization'!
initialize
"Initialize default values."
"Calculator initialize."
DefaultNoOfDigits _ 12! !
Calculator initialize!
Controller subclass: #CalculatorKeypadController
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-Calculator'!
!CalculatorKeypadController methodsFor: 'control defaults'!
controlActivity
"Pass control to a subView corresponding to a pressed keyboard key or to a mouse
button pressed, if any."
sensor keyboardPressed
ifTrue: [self processMenuKey]
ifFalse: [self controlToNextLevel]!
isControlActive
^((sensor keyboardPressed) | (view containsPoint: sensor cursorPoint))
& ((sensor blueButtonPressed not) & (sensor yellowButtonPressed not))!
processMenuKey
"The user typed a key on the keyboard. Give control to the subView that
is selected by this key."
| aView |
aView _ view subViewContainingCharacter: sensor keyboard.
aView ~~ nil
ifTrue: [aView controller sendMessage]
ifFalse: [view superView flash]! !
View subclass: #CalculatorView
instanceVariableNames: 'sevenSegForms cachedFormSize '
classVariableNames: 'KeyForms '
poolDictionaries: ''
category: 'Interface-Calculator'!
!CalculatorView methodsFor: 'initialize-release'!
initialize
super initialize.
sevenSegForms _ Array new: 12.! !
!CalculatorView methodsFor: 'displaying'!
displayError
"Display the error indication - a letter E."
((sevenSegForms at: 12) notNil and: [cachedFormSize = self currentFormSize])
ifFalse: [self newCachedForms].
(sevenSegForms at: 12) displayAt: self digitDisplayOrigin!
displayLeftDigits: aCollection
"Display, in seven segment form, the digits in aCollection,
starting from the left."
"The first field in the array is the right (least significant) digit."
| origin width |
((sevenSegForms at: 1) isNil or: [cachedFormSize ~= self currentFormSize])
ifTrue: [self newCachedForms].
width _ self digitBox width.
origin _ self digitDisplayOrigin.
1 to: aCollection size do: [ :count |
(sevenSegForms at: (aCollection at: count) + 1)
displayAt: origin + (count * width@0)]!
displayLeftPoint: aPosition
"Display a small black form representing the decimal point,
in a left justified manner."
| origin height width size form |
width _ self digitBox width.
height _ self digitBox height.
size _ width // 8 max: 2.
origin _ self insetDisplayBox origin +
(width * aPosition@0) +
((size negated // 2)@(self formBox height + self digitOffset y - size)).
form _ Form new extent: size@size.
form black.
form displayAt: origin!
displayMinus
"Display the minus sign."
((sevenSegForms at: 11) notNil
and: [cachedFormSize = self currentFormSize])
ifFalse: [self newCachedForms].
(sevenSegForms at: 11) displayAt: self digitDisplayOrigin!
displayRightDigits: aCollection
"Display, in seven segment form, the digits in aCollection,
starting from the right hand side."
"The first field in the array is the right (least significant) digit."
| origin width noOfDigits |
width _ self digitBox width.
origin _ self digitDisplayOrigin.
((sevenSegForms at: 1) isNil or: [cachedFormSize ~= self currentFormSize])
ifTrue: [self newCachedForms].
noOfDigits _ model noOfDigits + 1.
aCollection size to: 1 by: -1 do: [:count |
(sevenSegForms at: (aCollection at: aCollection size - count + 1) + 1)
displayAt: origin + (noOfDigits - count * width @ 0)]!
displayRightPoint: aPosition
"Display a small black form representing the decimal point,
suitable for a right justified display."
| origin height width size form position |
position _ model noOfDigits + 1 - aPosition.
width _ self digitBox width.
height _ self digitBox height.
size _ width // 8 max: 2.
origin _ self insetDisplayBox origin +
(width * position@0) +
((size negated // 2)@(self formBox height + self digitOffset y - size)).
form _ Form new extent: size@size.
form black.
form displayAt: origin!
displayView
"Display the displayValue in seven-segment form."
| digits value remainder count noOfDigits pointPosition trailingZeros |
model errorFlag ifTrue: [^self displayError].
value _ model displayValue.
value < 0 ifTrue: [
self displayMinus.
value _ value negated].
noOfDigits _ model noOfDigits.
digits _ OrderedCollection new: noOfDigits.
count _ 1.
remainder _ value - value truncated.
[value >= 10] whileTrue: [
digits addFirst: value \\ 10.
value _ value // 10.
count _ count + 1].
digits addFirst: value truncated.
count _ count + 1.
pointPosition _ count.
[(count <= noOfDigits) & (remainder ~= 0)] whileTrue: [
remainder _ remainder * 10.
value _ remainder truncated.
digits addLast: value.
remainder _ remainder - value.
count _ count + 1].
trailingZeros _ model trailingZeros.
[(count <= noOfDigits) & (trailingZeros > 0)] whileTrue: [
digits addLast: 0.
trailingZeros _ trailingZeros - 1.
count _ count + 1].
model leftJustify
ifTrue: [
self displayLeftDigits: digits.
self displayLeftPoint: pointPosition]
ifFalse: [
self displayRightDigits: digits.
self displayRightPoint: (count - pointPosition)].!
update: aParameter
self display! !
!CalculatorView methodsFor: 'private'!
currentFormSize
"Answer with the new current form size."
^self formBox extent!
digitBox
"Answers a rectangle which is the box used to divide up
the calculator digit display area."
| box |
box _ self insetDisplayBox copy.
box width: (box width // (model noOfDigits +1)).
^box!
digitDisplayOrigin
"Answer the origin for a digit display form for display."
^(self insetDisplayBox origin) + (self digitOffset)!
digitOffset
"Offset between digitBox and formBox."
^(self formBox origin) - (self digitBox origin)!
formBox
"Answers a rectangle which is the box used to display the
form representing calculator digits."
| box |
box _ self digitBox.
^box insetBy: (box width // 8 max: 3)@(box height // 8 max: 3)!
newCachedForms
"Re-calculates all the cached forms."
| size form halfHeight lineWidth |
size _ self currentFormSize.
lineWidth _ ((size x / 8) max: 2) roundTo: 2.
halfHeight _ ((size y / 2) + (lineWidth / 2)).
0 to: 11 do: [:count |
form _ Form new extent: size.
"Bottom Left Segment."
(#(1 3 4 5 7 9 10) includes: count) ifFalse: [
form fill: (0@(size y - halfHeight + 1) extent: (lineWidth@halfHeight))
rule: Form over
mask: Form black].
"Bottom Right Segment."
(#(2 10 11) includes: count) ifFalse: [
form fill: ((size x - lineWidth)@(size y - halfHeight + 1) extent: (lineWidth@halfHeight))
rule: Form over
mask: Form black].
"Bottom Segment."
(#(1 4 7 10) includes: count) ifFalse: [
form fill: (0@(size y - lineWidth) extent: ((size x)@lineWidth))
rule: Form over
mask: Form black].
"Center Segment."
(#(0 1 7) includes: count) ifFalse: [
form fill: (0@(size y - halfHeight) extent: ((size x)@lineWidth))
rule: Form over
mask: Form black].
"Top Left Segment."
(#(1 2 3 7 10) includes: count) ifFalse: [
form fill: (0@0 extent: (lineWidth@halfHeight))
rule: Form over
mask: Form black].
"Top Right Segment."
(#(5 6 10 11) includes: count) ifFalse: [
form fill: ((size x - lineWidth)@0 extent: (lineWidth@halfHeight))
rule: Form over
mask: Form black].
"Top Segment."
(#(1 4 10) includes: count) ifFalse: [
form fill: (0@0 extent: ((size x)@lineWidth))
rule: Form over
mask: Form black].
sevenSegForms at: count + 1 put: form
].
cachedFormSize _ size! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
CalculatorView class
instanceVariableNames: ''!
!CalculatorView class methodsFor: 'instance creation'!
open
"Create and schedule a new instance of the receiver on a new
Calculator."
"CalculatorView open."
self openOn: Calculator new!
openOn: aCalculator
"Create and schedule a new instance of the receiver on aCalculator."
"CalculatorView openOn: Calculator new."
| topView view |
topView _ StandardSystemView new.
topView label: 'Calculator'.
topView borderWidth: 2.
topView insideColor: Form lightGray.
topView minimumSize: 220@160.
view _ View new model: aCalculator controller: CalculatorController new.
topView addSubView: view.
self createSubViewsIn: view.
topView controller open! !
!CalculatorView class methodsFor: 'class initialization'!
initialize
"CalculatorView initialize."
| text form |
KeyForms _ Array new: 20.
0 to: 9 do: [ :number |
form _ Form new extent: 10@14.
text _ (number printString asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: 0@0 in: text rule: Form over.
KeyForms at: (number + 1) put: form].
form _ Form new extent: 10@14.
(Form dotOfSize: 8) displayOn: form at: 5@7.
KeyForms at: 11 put: form.
form _ Form new extent: 10@14.
text _ ('=' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: 0@0 in: text rule: Form over.
KeyForms at: 12 put: form.
form _ Form new extent: 10@14.
text _ ('+' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: 0@0 in: text rule: Form over.
KeyForms at: 13 put: form.
form _ Form new extent: 10@14.
text _ ('-' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: 0@0 in: text rule: Form over.
KeyForms at: 14 put: form.
form _ Form new extent: 10@14.
text _ ('X' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: -1@0 in: text rule: Form over.
KeyForms at: 15 put: form.
form _ Form new extent: 10@14.
text _ ('/' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: 0@0 in: text rule: Form over.
KeyForms at: 16 put: form.
form _ Form extent: 10@14 fromArray:
#(12288 12288 64512 64704
12672 13056 1536 3072
6144 12288 26560 51136 0 0) offset: 0@0.
KeyForms at: 17 put: form.
form _ Form extent: 10@14 fromArray:
# (0 1088 1088 640 256 256 512 35328
34816 20480 8192 20480 34816 34816 ) offset: 0@0.
KeyForms at: 18 put: form.
form _ Form new extent: 10@14.
text _ ('.' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: -2@0 in: text rule: Form over.
KeyForms at: 19 put: form.
form _ Form new extent: 10@14.
text _ ('C' asText emphasizeFrom: 1 to: 1 with: 11)
asParagraph asForm.
form copy: (text boundingBox) from: -1@0 in: text rule: Form over.
KeyForms at: 20 put: form.! !
!CalculatorView class methodsFor: 'class access'!
keyForms
"Answer with an array of forms used to display the keys."
"CalculatorView keyForms do: [ :each |
each displayAt: 100@100.
(Delay forSeconds: 1) wait]."
^KeyForms! !
!CalculatorView class methodsFor: 'private'!
addButtonViewsIn: aView
"Adds all the button subViews, for the calculator."
| offsets labels actions chars aButton aSwitchView |
offsets _ OrderedCollection new: 20.
#(15 45 75 105 135) do: [:i | offsets addLast: i@44].
#(15 45 75 105 135) do: [:i | offsets addLast: i@74].
#(15 45 75 105 135) do: [:i | offsets addLast: i@104].
#(15 45 75 105 135) do: [:i | offsets addLast: i@134].
labels _ OrderedCollection new: 20.
#(8 9 10 20 11) do: [:i | labels addLast: (KeyForms at: i)].
#(5 6 7 13 14) do: [:i | labels addLast: (KeyForms at: i)].
#(2 3 4 15 16) do: [:i | labels addLast: (KeyForms at: i)].
#(1 19 18 17 12) do: [:i | labels addLast: (KeyForms at: i)].
actions _ #(#add7 #add8 #add9 #clearEntry #clear
#add4 #add5 #add6 #add #subtract
#add1 #add2 #add3 #multiply #divide
#add0 #point #raiseTo #changeSign #equals).
chars _ #($7 $8 $9 $e $c
$4 $5 $6 $+ $-
$1 $2 $3 $* $/
$0 $. $^ $s $=).
1 to: 20 do: [ :i |
aButton _ Button newOff.
aButton onAction: [aView model perform: (actions at: i)].
aSwitchView _ SwitchView new model: aButton.
aSwitchView key: (chars at: i).
aSwitchView borderWidth: 2.
aSwitchView insideColor: Form white.
aSwitchView label: (labels at: i).
aSwitchView translateBy: (offsets at: i).
aSwitchView controller: IndicatorOnSwitchController new.
aView addSubView: aSwitchView.
].!
createSubViewsIn: aView
"Build subviews in aView."
| buttonView displayView |
aView window: (0@0 extent: 160@160).
displayView _ self new model: aView model controller: NoController new.
displayView borderWidth: 2.
displayView insideColor: Form white.
aView
addSubView: displayView
window: aView window
viewport: (2@2 corner: 158@32).
buttonView _ CalculatorKeypadView new
model: aView model
controller: CalculatorKeypadController new.
buttonView borderWidth: 2.
buttonView insideColor: Form gray.
aView
addSubView: buttonView
window: (2@34 corner: 158@158)
viewport: (2@34 corner: 158@158).
self addButtonViewsIn: buttonView.! !
CalculatorView initialize!
View subclass: #CalculatorKeypadView
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Interface-Calculator'!
!CalculatorKeypadView methodsFor: 'subView access'!
subViewContainingCharacter: aCharacter
"Answer the receiver's subView that corresponds to the key, aCharacter.
Answer nil if no subView is selected by aCharacter."
self subViews reverseDo:
[:aSubView |
(aSubView containsKey: aCharacter asLowercase) ifTrue: [^aSubView]].
^nil! !